home *** CD-ROM | disk | FTP | other *** search
Text File | 1993-09-20 | 3.3 KB | 119 lines | [TEXT/MPS ] |
- C FaceWare 2.2 Initialization & Dispatching Procedures
- C ©FaceWare 1989-93. All Rights Reserved.
-
- C NOTE: To compile this file as a separate object, you'll need
- C to add the "!!M Inlines.f" directive seen in the demo program.
-
- SUBROUTINE fJumpIt(theProc,thePtr)
- integer*4 thePtr
- call theProc(%val(thePtr))
- return
- end
-
- SUBROUTINE FaceIt(xPtr,m1,m2,m3,m4,m5)
- implicit none
- C NOTE: If you use the "!!G" directive for precompiled globals, add
- C our FaceStorLF.inc globals to yours and then remove following line
- include 'FaceStorLF.inc'
- record /FaceRec/ fRec
- common/FaceStuff/fRec
- structure /HeadRec/
- integer*4 addr
- integer*2 baseID
- integer*2 versID
- integer*2 message
- integer*2 resID
- integer*4 fPtr
- end structure
- pointer /HeadRec/ thePtr
- character*4 restype
- integer*4 xPtr,m1,m2,m3,m4,m5,i,fPtr
- thePtr = xPtr
- fPtr = %loc(fRec)
- if (m1 = -61) then
- if ((m4 > -1).and.(.not.BTEST(m4,0))) then
- !ignore spurious mouse & key events
- call FlushEvents(%val(int2(62)),%val(int2(0)))
- end if
- restype = 'FCMD' !find LoadIt or quit to Finder
- if (GetResource(%val(restype),%val(int2(1000))) = 0) then
- if (OpenResFile(%val(trim(fRec.uName))) < 0) stop
- end if
- fRec.fFlags = m2 !store FaceIt bit flags
- fRec.xEntries = m5 !store # of table entries
- thePtr = fPtr
- if (m3 > -1) then !call LoadIt to expand heap?
- call PrepIt(thePtr,m3,0,0,thePtr)
- call fJumpIt(%val(long(thePtr)),thePtr)
- end if
- call PrepIt(thePtr,1100,22,0,thePtr) !setup fRec header
- call PrepIt(thePtr+1002,1210,22,0,thePtr) !setup uRec header
- call PrepIt(thePtr+1634,1200,22,0,thePtr) !setup vRec header
- fRec.fHead(6) = m4 !store environment type
- fRec.uHead(6) = 2 !establish string type
- thePtr = 0
- if (m4 < -3) return
- end if
- if (m1 = -62) then
- call PrepIt(m2,m3,m4,m5,fPtr)
- else if ((m1 < 0).and.(m1 > -11)) then
- i = (4 * (-1 - m1))
- fRec.xTable(1+i) = m2
- fRec.xTable(2+i) = m3
- fRec.xTable(3+i) = m4
- fRec.xTable(4+i) = m5
- else
- if (thePtr = 0) then !call to default module?
- thePtr = fPtr + 1002
- else if (thePtr^.fPtr <> fPtr) then
- fRec.cControl = thePtr !call to control driver?
- thePtr = fPtr + 1634
- end if
- thePtr^.message = 0
- fRec.uCommand = m1 !pass Command & Params
- fRec.uParam(1) = m2
- fRec.uParam(2) = m3
- fRec.uParam(3) = m4
- fRec.uParam(4) = m5
- call fJumpIt(%val(long(thePtr)),thePtr) !jump to FCMD
- end if
- end
-
- SUBROUTINE PrepIt(x,b,v,r,f)
- implicit none
- C NOTE: If you use the "!!G" directive for precompiled globals, add
- C our FaceStorLF.inc globals to yours and then remove following line
- include 'FaceStorLF.inc'
- record /FaceRec/ fRec
- common/FaceStuff/fRec
- structure /HeadRec/
- integer*4 addr
- integer*2 baseID
- integer*2 versID
- integer*2 message
- integer*2 resID
- integer*4 fPtr
- end structure
- pointer /HeadRec/ x
- integer*4 b,v,r,f,i
- character*4 restype
- restype = 'FCMD'
- x^.addr = long(GetResource(%val(restype),%val(int2(1000))))
- x^.baseID = b
- x^.versID = v
- x^.message = 0
- x^.resID = r
- x^.fPtr = f
- if (fRec.xEntries > 0) then
- do i = 0, fRec.xEntries-1
- if (b = fRec.xTable(1 + 4*i)) then
- if (v = fRec.xTable(2 + 4*i)) then
- if (0 <> fRec.xTable(4 + 4*i)) then
- x^.addr = fRec.xTable(4 + 4*i)
- end if
- end if
- end if
- end do
- end if
- end
-